.TITLE DCCHE - $CACHE ENTRY .IDENT /05.00/ .IF DF D$$CHE ; ; Copyright (c) 1995-1999 by Mentec, Inc., U.S.A. ; All rights reserved ; ; All rights reserved. ; ; Original author: ; John Gemignani ; ; Modified by: ; ; D. P. Rabahy 06-Mar-85 01.01 ; ; Re-mastered for RSX-11M-PLUS V4.4 by: ; ; L. B. McCulley 29-Dec-91 4.00 ; D. Carroll 05-August-1992 4.01 ; L. B. McCulley 8-Aug-92 4.01a ; D. Carroll 10-October-1992 4.02 ; D. Carroll 28-October-1992 4.03 ; D. Carroll 13-Nov-1992 4.04 ; ; Modified for RSX-11M-PLUS V4.6 by: ; ; D. Carroll 8-Jan-1996 05.00 ; DC430 - Include support for 32-bit LBNs ; ; ; This module contains the various entry points into the cache code. The ; executive transfers control to the cache via entry point $CACHE, from ; $DRQRQ in module DRSUB. The entry point at $CACHE must be at 120000 for ; the transfer of control from the executive. (Note that other entry paths ; are possible when the cache uses internal I/O mechanism or the fork list) ; ; Entry point $XPLOA is called by the LOAD utility to load the cache code ; EXP. Likewise, entry point $XPUNL is called by UNLOAD to remove the cache ; code. This requires special handling, since you must guarantee that this ; is not being used. A recommended way to do this is to check the cache ; fields of the UCBX for all disks on the system. If the appropriate cache ; are NOT on, then the code has no partitions in the system which are active ; ; Note that the EXP hookpoints ($XPLOA and $XPUNL) are called in APR6. ; Therefore, position-independent code is required, with absolute references ; corrected by subtracting 20000 from the target addresses. The cache code ; built for APR5 (120000->137777), and the subtraction of the 020000 will ; the 140000-157777 references to the proper address range. ; .MCALL PCBDF$ PCBDF$ ;Define partition control block .SBTTL $CACHE - Main entry point from $DRQRQ ; ; The presence of the packet is guaranteed (driver ; kick-starts will bypass the dispatching routine). ; The UCB and SCB are accessible via R5 and R4 ; respectively. The caller's mapping has been saved ; on the stack above the return address to $DRQRQ. ; $CACHE:: CALLR DCPHS1 ; invoke Phase I cache dispatcher .SBTTL Executive external partition routines .SBTTL + $XPLOA - "LOAD /EXP=" entry point. ; ; This routine (module, and whole EXP for that matter) is ; mapped in APR6 (140000->157777). The stack contains the ; return address to LOAD, and the address above that is the ; PCB address of the partition which LOAD created and copied ; us into. LUN 1 is assigned to the issuer's console (TI:). ; We are NOT in system state. Status is returned via the ; C-bit: CC is success, CS is failure. ; $XPLOA:: TST @#$DRCHE ;Already loaded? BNE 10$ ;Yes if NE MOV 2(SP),R0 ;Else get our PCB address MOV P.REL(R0),@#$DRCHE ;And tell the exec about it TST (PC)+ ;Return success 10$: SEC ;Else error if loaded RETURN ;Back to LOAD .SBTTL + $XPUNL - "UNLOAD /EXP=" entry point. ; ; This routine (module, and whole EXP for that matter) is ; mapped in APR6 (140000->157777). The stack contains the ; return address to UNLOAD. LUN 1 is assigned to the ; issuer's console (TI:). We are NOT in system state. ; Status is returned via the C-bit: CC is success, CS is ; failure. ; ; NOTE: The use of the LOA/UNL EXP function is designed only for ; development use, and any other use could be potentially ; hazardous. This code does not scan the database to insure ; that there are no devices with caching active, and as such ; this mechanism should not be used. ; $XPUNL:: CLR @#$DRCHE ;Wipe out APR bias to unload RETURN ;And return with CC .SBTTL Dispatch incoming I/O operations from $DRQRQ exec calls .SBTTL + DCPHS1 - dispatcher (Start phase 1 operations) ;+ ; **-DCPHS1 - Cache dispatcher entry point ; ; Passed: ; R1 -> I/O packet ; R5 -> UCB ; ; Returned: ; R0 contents lost ; ; Control is passed to the appropriate phase-I routine ; ; Action: ; This routine is used to dispatch the I/O packet to ; the appropriate action routines. The UCBX is mapped ; before beginning processing, in order to make the ; context handy, and to verify that the UCBX is present. ; (Disk UCBs without UCBXs are either offline, or don't ; have one due to a lack of secondary pool, and as such ; cannot support data caching.) ; ; All I/O functions except IO.STC require the cache to be ; activated in order for dispatching (since IO.STC is used ; to activate the cache), thus IO.STC is dispatched before ; cache is checked to make sure it is active. ; ; Other I/O functions are dispatched in a logical order. ; ; IO.LOV and IO.LDO must be checked next, because they are ; subfunctions of IO.RLB and subfunction bits cannot be masked ; off before recognition of overlay loads. ; ; After overlay loads are recognized, the subfunction bits are ; masked off to eliminate confusion with such things as IO.RLC ; and IO.WLC. ; ; Then the basic read and write functions (IO.RLB and IO.WLB) ; are checked. ; ; The "bypass" subfunction bits (IQ.X, IQ.S, IQ.Q) will force ; cache to be bypassed for reads, but writes must still be seen ; by cache to allow flushing stale extents, so these are tested ; after recognition of IO.RLB functions. ; ; While processing in phase I, this module will be available in ; Kernel-D space (if supported), until the cache partition is ; first mapped. This is intended to aid in the initial dispatch ; of the various functions. ; ; The mapping structure of phase I goes as follows; with the ; following mapping initially set up; ; ; Kernel-I space Kernel-D Space ; ; +------------------+ +--------------------+ ; ! DCM11M code ! ! DCM11M code ! ; !------------------! !--------------------! ; ! Don't care ! ! UCBX ! ; !//////////////////! !////////////////////! ; ; ; Once the data cache partition is mapped, the structure appears ; as the following; ; ; +------------------+ +--------------------+ ; ! DCM11M code ! ! Cache Partition ! ; !------------------! !--------------------! (Pool area) ; ! Don't care ! !Cache Partition/UCBX! ; !//////////////////! !////////////////////! ; ; For I-space only systems, the general layout is; ; ; ; +--------------------+ ; ! DCM11M code ! ; !--------------------! ; !Cache Partition/UCBX! ; !////////////////////! ; ;- DCPHS1: CALL $SAVNR ; save non-volatile registers .IF DF K$$DAS MOV KINAR5,KDSAR5 ; map the region in D-space as well .ENDC ;DF,K$$DAS MP.UCBX ; Map the UCBX into APR6 BEQ DCRJCT ; None present if EQ, no caching .IF DF S$$HDW&S$$HLS BIT #1,I.IOSB+4(R1) ; does this have an IIOC planned? BEQ 10$ ; if EQ, nope, continue CMP @#KINAR5,I.IOSB+2(R1) ; is that IIOC scheduled for us? BEQ DCRJCT ; yes, forward on to the driver .ENDC ;DF,S$$HDW&S$$HLS 10$: MOVB I.FCN+1(R1),R0 ; get the high order function code CMPB R0,#IO.RLB/256. ; is this a control function? BLOS 20$ ; if LO, nope, trasnfer, check activity CMP I.FCN(R1),#IO.STC ; is this a full IO.STC operation? BNE DCRJCT ; if NE, nope, send it to the driver CALL DCCTL1 ; dispatch control function BCS DCRJCT ; send to phase II TST R1 ; any packet left? BNE DCFORK ; if NE, yes, check fork BR DCEXIT ; and finish up 20$: DEC R0 ; normalize index to RLB/WLB BMI DCRJCT ; if MI, was IO.KIL BITB #XC.ACT, APR6.BASE+X.CSTS ; Cache active for this unit? BEQ DCRJCT ; No if EQ, pass to the driver CMP I.TCB(R1),$RCTPT ; is this request from RCT? BEQ DCRJCT ; don't even think of syncronizing BITB #X2.DEA, APR6.BASE+X.CST2 ; Cache rundown in progress? BEQ 30$ ; No, go ahead and process CALL Q2DRVR ; Queue, send to driver after rundown BR DCFORK ; and finish rundown 30$: ASL R0 ; convert function to word index CALL @DCDISP(R0) ; and dispatch the function BCC DCFORK ; If Phase 1 accepted cache operation BCS DCRJCT ; ...see if Phase 2 required now ; ...else return flag to call driver DCEXIT: CLR R1 ; tell $DRQRQ we handled it DCRJCT: RETURN ; we still haven't returned ther DCUNK: SEC ; flag to pass to driver RETURN ; and finish processing DCDISP: .WORD DCW1 ; IO.WLB (Write phase I) .WORD DCRLB ; IO.RLB/IO.LOV ;+ ; **-DCRLB -- Process IO.RLB, and its subfunctions ; ; This routine will seperate out the various types ; of read functions, namely (IO.RLB, IO.LOV, IO.LDO, and IO.SCF) ; ;- DCRLB: MOV I.FCN(R1),R0 ; Get the function code CMP #IO.LOV,R0 ; Load I-space overlay? BEQ 20$ ; Yes if EQ CMP #IO.LDO,R0 ; Load D-space overlay? BNE 30$ ; No if NE (or, Yes if EQ ) 20$: CALLR DCOV1 ; Invoke load overlay phase I 30$: BIT #CHEBYP,R0 ; Should read be bypassed? BEQ 35$ ; no bypass function requested CALLR CHEPUR ; check for deferred extent overlap 35$: ; reference label .IF DF, S$$HDW TST U.UMB(R5) ; is this unit being shadowed? BEQ 40$ ; no, go do it CMP #IO.SCF,R0 ; is this a shadow copy function BEQ DCUNK ; yes, don't cache it! .ENDC ; S$$HDW 40$: CALLR DCR1 ; Invoke read phase I .SBTTL Phase II operations fork queue entry .SBTTL + DCFORK - Start Phase II Cache Process ;+ ; Routine DCFORK is responsible for obtaining a unit of work ; from the packet queue and initiating Phase II processing ; using the system FORK queue. ; ; Passed: ; ; R5 -> UCB (used to find cache region to map). ; ; The packet queue for Phase II processing is located at ; H.PKTQ in the cache region. ; ; The queue contains the User Request Packet (URP, the system I/O ; packet passed to the data cache code from $DRQRQ for a user request. ; ; During Phase I processing of transfer operations (reads and writes ; there was a Cache Request Packet (CRP) allocated in cache internal ; pool (or system pool) for request context storage. I.AADA in the ; URP points to to the associated CRP. The original I/O packet ; contents from the URP are saved in the CRP, and the URP is updated ; (and occasionally refreshed) as cache processing progresses. This ; routine does not care about the CRP except when passing packets to ; the driver for completion during deactivation rundown. ; ; There is a special case where an I/O packet is passed to fork ; processing which does not have a CRP. This is when a given request ; has indicated that it should bypass data cache, however there are ; extents which must be addressed prior to forwarding to the driver. ; In this case, the TCB address in the I/O packet is set odd, and ; that is used as a flag to continue processing overlapping extents. ; ; ; Returned: ; ; This routine is used to start up a Phase II cache process. ; RETURNing to our caller will do the proper thing. Our caller is ; of no concern to us; we are "the system" (or believe that we are ; when we reach this point. ; ; Routine DCFORK is responsible for synchronizing us with other ; system (and possibly cache ioc) activity using the system fork ; mechanism. Here we setup and queue a fork block if there is any ; work for Phase II. ; ; This code will execute a fork each time through the Phase II ; dispatching code. This is performed to allow any outstanding ; fork-level processes to execute before or between Phase II runs. ; ; In a multi-processor environment, the code will attempt to allow ; another processor to run, by setting up a UNIBUS Run mask which ; if the logical "or" of all other pending fork blocks, which may ; be 0. ; ; The fork block is allocated from pool (DSR) when it is ; first needed, and kept as long as the cache region is ; active. There is one fork block per active cache region. ; It is deallocated in DCCTL deactivation when deactivation ; completes for the last unit cached in the region. ;- .ENABL LSB DCFRK0::BISB #CS.DNF,APRD.BASE+H.CSTS ; insure we fork BR 10$ ; and skip the mapping DCFORK::MP.PAR ; ensure cache par is mapped 10$: CMP APRD.BASE+H.PAVL,#3 ; is our pool constant still there? BNE 60$ ; if NE, nope, partition not mapped TST APRD.BASE+H.PKTQ ; anything queued? BEQ 50$ ; If EQ, nothing queued, exit now MOV APRD.BASE+H.FRK,R0 ; get fork block ptr in cache header BNE 110$ ; got one, use it! ;+ ; At this point, we must allocate a fork block for use while this ; region is active. The fork block layout is as follows; ; ; +---------------------------+ ; ! UNIBUS Run Mask ! (mP systems only) ; !---------------------------! ; ! Fork list link word ! ; !---------------------------! ; ! PC of fork routine ! (Address of DCPHS2) ; !---------------------------! ; ! R5 of fork routine ! (UCB address of device) ; !---------------------------! ; ! R4 of fork routine ! (I/O packet to be processed) ; !---------------------------! ; !KINAR5 bias of fork routine! ; +---------------------------+ ;- MOV #<6.*2>,R1 ;Attempt to allocate a fork block CALL $ALOCB ;From system pool BCS 50$ ;If CS, MAJOR PROBLEM: ignore for now ; R0 -> Newly allocated pool block CLR (R0)+ ;URM=0; any processor can do it MOV R0,APRD.BASE+H.FRK ; save fork block ptr in cache header MOV @#KINAR5,10(R0) ; store our APR bias BR 120$ ; go fork into phase II 50$: BICB #CS.DNF,APRD.BASE+H.CSTS ; allow to skip fork again BR DCEXIT ; and finish up 60$: FATAL$ BE.IDC ; region not mapped 110$: TST 2(R0) ; see if it is in use (use PC as flag) BNE 50$ ; yes, just return, we'll be back 120$: MOV APRD.BASE+H.PKTQ,R4 ; Remove this one from the queue ;URP address returned in R4 from BIT #1,I.TCB(R4) ; is this a purge request? BNE 125$ ; if NE, yes, doesn't have a CRP CMPB I.FCN+1(R4),#IO.STC/256. ; or is this a control function? BEQ 125$ ; if EQ, yes, no CRP present here CMP @I.CRP(R4),R4 ; is the CRP coherent? BEQ 125$ ; if EQ, yes, continue ... FATAL$ BE.IDC ; CRP is corrupted 125$: MOV (R4),APRD.BASE+H.PKTQ ; link to next one BNE 130$ ; Not last packet if NE MOV #APRD.BASE+H.PKTQ,APRD.BASE+H.PKTQ+2 ; update "last" 130$: CACHE$ BYPASS ; insure we see the real thing TST $FRKHD ; any fork processing pending? BNE 140$ ; if NE, we should fork BITB #CS.DNF,APRD.BASE+H.CSTS ; can we skip the fork? BNE 140$ ; if NE, nope, we have to fork ;+ ; At this point, there is no reason to execute a fork, since we are in ; no rush to return to our caller, and we can continue execution. ;- CACHE$ RESTOR ; unbypass cache .IF DF K$$DAS MOV @#KINAR5,@#KISAR5 ; remap ourselves into kernel-D space .ENDC ;DF,K$$DAS MOV R0,R3 ; copy fork block to R3 TST (R3)+ ; and advance to the PC address BR DCPHS2 ; and enter into phase II 140$: CACHE$ RESTOR ; unbypass cache BICB #CS.DNF,APRD.BASE+H.CSTS ; remove our phase I interlock ADD #6,R0 ;Advance to R4 storage MOV R4,(R0) ;set URP pointer returned in R4 MOV R0,R4 ;Set fork blk ptr for call to $FORK1 CLR R1 ;make sure DRQRQ knows we accepted CALL $FORK1 ;Queue the fork block and return ; to process phase II operations .DSABL LSB .SBTTL PHASE II OPERATIONS DISPATCHER .SBTTL + DCPHS2 - dispatch Phase II Cache Process .SBTTL + DCEXIT - finished cache processing for now ;+ ; Routine DCPHS2 is responsible for obtaining a unit of work ; from the packet queue and passing it to the appropriate ; processing routine. ; ; The packet queue for Phase II processing is located at ; H.PKTQ in the cache region. The queue contains the User Request ; Packet (URP, the system I/O packet passed to the data cache code ; from $DRQRQ for a user request. In Phase I of transfer operation ; there was a Cache Request Packet (CRP) allocated in cache internal ; pool for request context storage. I.AADA in the URP points to to the ; associated CRP. The original I/O packet contents from the URP are ; saved in the CRP, and the URP is updated (and occasionally refreshed ; as cache processing progresses. The I/O function code determines the ; address to which control should be passed when the packet is dequeued ; and dispatched here. ; ; In some cases, the URP will not have a CRP allocated, and these ; requests are queued to ensure the integrity of cache with respect ; to a given I/O request. If an I/O request includes bypass bits ; to read underneath data cache, then the deferred extents will be ; written to disk. ; ; ; Start Phase II Cache Process ; ; Context: ; R3 -> PC stored in fork block ; R4 -> URP from cache phase 2 queue ; ; Note: Until the first MP.PAR invocation, this code is mapped ; in both I/D space on systems which support kernel-I/D ; space. ;- DCPHS2: CLR (R3) ; clear to show fork block now available ; R4 -> URP passed across fork MOV R4,R1 ; set conventional URP pointer MOV I.UCB(R1),R5 ; set up conventional UCB ptr to MP.UCBX ; map UCBX for now MOV #DCFORK,-(SP) ; set up a return address MOVB I.FCN+1(R1),R0 ; extract the high byte of the function CMPB R0,#IO.STC/256. ; is this a control function? BLO 20$ ; if LO, nope, must be transfer BNE DSPERR ; if NE, fatal, dispatch error CALLR DCCTL2 ; assume must be phase 2 of ctl 20$: BIT #1,I.TCB(R1) ; are we in a purge operation? BNE 30$ ; yes, continue scan BITB #X2.DEA,APR6.BASE+X.CST2 ; are we being deactivated BEQ 40$ ; no, continue processing TST I.ACED(R1) ; CED attached? (eg, I/O completion) BNE 40$ ; yes, just let it complete MP.PAR ; map cache paritition CALL RLSCRP ; release CRP, refresh URP CALLR Q2DRVR ; queue to driver on completion 30$: CALLR PURPH2 ; continue phase II purge 40$: CMP R0,#IO.RLB/256. ; only two possibilities allowed BHI DSPERR ; dispatch error ASL R0 ; convert to a word index CALLR @DCDSP2(R0) ; and dispatch by function DCDSP2: .WORD DSPERR ; IO.KIL .WORD DCW2 ; IO.WLB (Write phase II) .WORD DCR2 ; IO.RLB, IO.LOV, IO.LDO (phase II) DSPERR: FATAL$ BE.IFC ; Invalid function code bugcheck .SBTTL Common Phase I processing routines .SBTTL + PURCHE - purge out extents for read-under cache ;+ ; PURCHE -- This routine will purge out any extents which may overlap ; a request, such that if a request is posted which either has bypass bits ; set, or is too large, it will not encounter stale cache data ... ; ; If the request is a write, all affected extents will be purged ; ; Input: ; R1 - URP, w/o CRP ; R5 - UCB ; ; Output: ; CC-C set, forward to driver ; CC-C clr, URP tied to given extent ; ;- PURCHE::MP.UCBX ; map cache partition BITB #XC.DFR, APR6.BASE+X.CSTS ; are deferred writes possible? BNE 5$ ; if NE, yes, must scan CMPB I.FCN+1(R1),#IO.RLB/256. ; is this a read? BEQ 30$ ; if EQ, yes, skip this 5$: CALL SEARCH ; search for any extents BCS 50$ ; no overlaps, finish up 10$: BITB #ES.WDF,E.STAT(R0) ; is this extent deferred BNE 15$ ; we must purge this extent CMPB I.FCN+1(R1),#IO.WLB/256. ; is this a write request BNE 20$ ; if NE, continue the scan ;+ ; This is a bit messy, since we have pending extents in cache, which ; must be flushed, however, we must queue the block through cache so ; that we can allow the extents to be purged. ;- 15$: BIS #1,I.TCB(R1) ; flag that purge is active MOV I.ACED(R1),-(SP) ; save the old attach ptr CLR I.ACED(R1) ; make it look free CALL ATTCED ; attach to the CED MOV (SP)+,I.ACED(R1) ; restore CED pointer BCS 40$ ; await phase II arrival BISB #ES.DEL,E.STAT(R0) ; flag to delete MOV E.LNXT(R0),-(SP) ; save the next extent MOV I.ACED(R1),-(SP) ; save real attachment info MOV R0,I.ACED(R1) ; and show we are attached CALL DETCED ; force a write of this CED BCS 60$ ; extent I/O is pending MOV (SP)+,I.ACED(R1) ; restore attachment pointer MOV (SP)+,R0 ; get the next CED BIC #1,I.TCB(R1) ; allow continuation BR 30$ ; and continue the scan 20$: MOV E.LNXT(R0),R0 ; get the next extent 30$: SEC ; flag to forward to driver BEQ 50$ ; if EQ, no defers to copy CMP R3,E.LBNL+2(R0) ; does this extent overlap ;DC430 BLO 50$ ; if LO, nope, send to driver ;**-1 BHI 10$ ; if HI, yes, check this CMP R2,E.LBNL(R0) ; how about the low order BHIS 10$ ; if HIS, yes, check this RETURN ; w/ CC-C set, all done 40$: CLC ; we are queued to a CED 50$: RETURN ; to caller 60$: CALL ATTCED ; re-attach to the CED MOV (SP)+,I.ACED(R1) ; restore attachment pointer TST (SP)+ ; clean stack RETURN ; and await phase II .SBTTL + CHEPUR, Common dispatch to remove extents in contention ;+ ; **-CHEPUR- Common routine from read/write to purge contending extents ; ; Input: ; Phase I processing context ; ; Output: ; CC-C clear, cache has extent attached ; CC-C set, forward request to driver via phase I exit ; ;- CHEPUR::CALL PURCHE ; purge out extents BCS 10$ ; if CC-C set, forward to driver BISB #CS.DNF,APRD.BASE+H.CSTS ; insure that we fork CLR R1 ; insure no packet to confuse 10$: RETURN ; to caller .SBTTL + PURPH2, Continue phase II purge processing ;+ ; **-PURPH2- Purge phase II, continue extent scan ; ; This routine is entered immediately after DCPHS2 to continue ; the scan for extents which overlap a given I/O request. It is ; expected that this routine will never be required, and is included to ; bullet proof the test cases which create paranoid overlap of deferred ; extents ... ; ; Input: Normal Phase II setting, immediately after starting ; phase II ; ;- PURPH2::CALL PURCHE ; look for more overlap ... BCC 10$ ; if CC, we are tied to a CED BIC #1,I.TCB(R1) ; reset our purge flag for now . CALLR .DRQRQ ; and forward the request to the 10$: RETURN ; to caller .SBTTL + INICTX, Initialize statistics context ;+ ; **-INICTX- Initialize statistics context ; ; This routine will determine the type of I/O request which has ; posted, and return the max extent size, statistics offset, and status ; bits to continue through Phase I. ; ; Input: ; R1 - URP ; R5 - UCB address ; Cache code mapped in KISAR5 ; UCBX mapped ; ; Output: ; R0 - Pointer to context for I/O request ; 0(R0) - bit to test ; 2(R0) - max extent size pointer ; 4(R0) - Statistics block address ; CC-C clear, not virtual I/O ; CC-C set , virtual I/O ;- INICTX::MOV #IOFNC+2,R0 ; assume logical I/O BITB #,U.STS(R5) ; check mounted status BNE 30$ ; if NE, not mounted, or foreign ; treat as logical I/O TSTB I.EFN(R1) ; is this virtual I/O BMI 20$ ; if MI, this is virtual I/O CMP I.TCB(R1),U.ACP(R5) ; is issuing task ACP for this device BNE 30$ ; if NE, nope, logical I/O ; ; The following code determines if context switching is disabled since it is ; when F11ACP has I/O issued on behalf of a user task due to a extent ; crossing (i.e. mapping failure). Otherwise, it is considered directory I/O. ; TSTB $CXDBL ; context switch enabled? BNE 20$ ; if NE, then virtual I/O TST -(R0) ; this is directory I/O BR 40$ ; and join common code 20$: TST (R0)+ ; advance to virtual stats SEC ; set carry BR 40$ ; and finish up 30$: CLC ; insure carry clear (not virtual I/O) 40$: MOV (R0),R0 ; get the stats context RETURN ; to caller (DCR1/DCW1) ;+ ; Function code local data ;- IOFNC: .WORD IODIR,IOLOG,IOVIR ; types of reads IODIR: .WORD XC.DIR, APR6.BASE+X.XDIR, APR6.BASE+S.DIR IOLOG: .WORD XC.LOG, APR6.BASE+X.XLOG, APR6.BASE+S.LOG IOVIR: .WORD XC.DAT, APR6.BASE+X.XDAT, APR6.BASE+S.DAT .PSECT $PATCH PATCH:: .WORD 0 ; .ENDC ; .IF DF D$$CHE .END